GrowDBHech2o Subroutine

public subroutine GrowDBHech2o(cc, hdmin, hdmax, ws, dws, DBH, height, tree_density, wood_density, age, maxage)

update DBH and height tree according to ech2o model by Maneta

Arguments

Type IntentOptional Attributes Name
real(kind=float), intent(in) :: cc

canopy cover

real(kind=float), intent(in) :: hdmin

H/D ratio in carbon partitioning for low density

real(kind=float), intent(in) :: hdmax

H/D ratio in carbon partitioning for high density

real(kind=float), intent(in) :: ws

stem biomass (t/ha)

real(kind=float), intent(in) :: dws

stem biomass increment (t/ha)

real(kind=float), intent(inout) :: DBH
real(kind=float), intent(inout) :: height
real(kind=float), intent(in) :: tree_density

tree density (trees/ha)

real(kind=float), intent(in) :: wood_density

wood density (kg/m3)

real(kind=float), intent(in) :: age

tree age (year)

real(kind=float), intent(in) :: maxage

tree max age (year)


Variables

Type Visibility Attributes Name Initial
real(kind=float), public :: dDBH
real(kind=float), public :: delta_tree_mass

tree mass increment (kg/tree)

real(kind=float), public :: dheight
real(kind=float), public :: fhd

grow factor that depends on the height-to-diameter ratio


Source Code

SUBROUTINE  GrowDBHech2o &
!
(cc, hdmin, hdmax, ws, dws, DBH, height, tree_density, wood_density, age, maxage) 
 
    
IMPLICIT NONE

!arguments with intent(in):
REAL (KIND = float), INTENT(IN) :: cc !! canopy cover
REAL (KIND = float), INTENT(IN) :: hdmin !! H/D ratio in carbon partitioning for low density
REAL (KIND = float), INTENT(IN) :: hdmax !! H/D ratio in carbon partitioning for high density
REAL (KIND = float), INTENT(IN) :: ws !! stem biomass (t/ha)
REAL (KIND = float), INTENT(IN) :: dws !! stem biomass increment (t/ha)
REAL (KIND = float), INTENT(IN) :: tree_density !! tree density (trees/ha)
REAL (KIND = float), INTENT(IN) :: wood_density !! wood density (kg/m3)
REAL (KIND = float), INTENT(IN) :: age !! tree age (year)
REAL (KIND = float), INTENT(IN) :: maxage !!tree max age (year)

!arguments with intent inout
REAL (KIND = float), INTENT(INOUT) :: DBH  !diameter at brest height (cm)
REAL (KIND = float), INTENT(INOUT) :: height  !tree height (m)

!local declarations
REAL (KIND = float) :: delta_tree_mass !!tree mass increment (kg/tree)
REAL (KIND = float) :: fhd !! grow factor that depends on the height-to-diameter ratio
REAL (KIND = float) :: dDBH !DBH increment (cm)
REAL (KIND = float) :: dheight !height increment (m)

    
!-------------------------------end of declarations----------------------------

!compute mass increment per tree
delta_tree_mass = dws / tree_density * 1000. ! mass increment per tree (kg)

!set grow factor
IF (height / DBH >= hdmin .AND. cc < 0.95) THEN
    fhd = hdmin
ELSE IF (height / DBH <= hdmax .AND. cc >= 0.95 .AND. age < maxage / 2) THEN
    fhd = hdmin
ELSE IF (height / DBH <= hdmax .AND. cc >= 0.95 .AND. age > maxage / 2 ) THEN
    fhd = hdmax
ELSE IF (height / DBH < hdmin) THEN
    fhd = hdmax
ELSE IF (height / DBH > hdmax) THEN
    fhd = 0.5 * hdmin
ELSE IF ( age > 0.7 * maxage) THEN
    fhd = 0.
END IF

!compute DBH increment
dDBH = 4. * delta_tree_mass / ( wood_density * pi * (DBH / 100.)**2. * ( 2. * height / (DBH / 100.) + fhd * 100. ) ) * 100.


!compute tree height increment
dheight = dDBH * fhd

!update dbh and height tree
 DBH = DBH + dDBH
 height = height + dheight

!write(*,*) dDBH, dheight
!pause


RETURN
END SUBROUTINE GrowDBHech2o